ReservoirSaveStatus Subroutine

public subroutine ReservoirSaveStatus(pathOut, time)

Save reservoirs status into file

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: pathOut
type(DateTime), intent(in), optional :: time

Variables

Type Visibility Attributes Name Initial
type(Reservoir), public, POINTER :: currentReservoir
integer(kind=short), public :: i
character(len=100), public, ALLOCATABLE :: row(:)
character(len=300), public :: string
type(Table), public :: tab

Source Code

SUBROUTINE ReservoirSaveStatus &
  !
  ( pathOut, time )

IMPLICIT NONE


!arguments with intent(in):
CHARACTER ( LEN = *), INTENT (IN) :: pathOut
TYPE (DateTime), OPTIONAL, INTENT (IN) :: time

! local declarations:
TYPE (Table) :: tab
CHARACTER (LEN = 300) :: string
CHARACTER (LEN = 100), ALLOCATABLE :: row (:)
INTEGER (KIND = short) :: i
TYPE (Reservoir), POINTER :: currentReservoir !points to current reservoir
!-------------------------------end of declaration-----------------------------

!create new table for reservoir stage
CALL TableNew ( tab )

!populate table
string = 'reservoir stage'
CALL TableSetId ( tab, string)

IF ( PRESENT (time) ) THEN
  timeString = time
  string = 'reservoir stage at: ' // timeString
ELSE
  string = 'reservoir stage at the end of simulation' 
END IF
CALL TableSetTitle ( tab, string)

!Allocate variables
CALL TableSetRowCol ( tab, nReservoirs, 2 )
IF ( ALLOCATED ( row ) ) THEN
    DEALLOCATE ( row )
END IF
ALLOCATE ( row (2) )

!set column header and unit
CALL TableSetColHeader (tab, 1, 'id')
CALL TableSetColHeader (tab, 2, 'stage')

CALL TableSetColUnit (tab, 1, '-')
CALL TableSetColUnit (tab, 2, 'm')

!fill in rows
currentReservoir => pools

DO i = 1, nReservoirs
     !id
     row (1) = ToString (currentReservoir % id)
     !stage
     row (2) = ToString (currentReservoir % stage)
     
     currentReservoir => currentReservoir % next
     
     CALL TableFillRow (tab, i, row)
END DO

IF (PRESENT(time)) THEN
	timeString = time
	timeString = timeString (1:19) // '_'
	timeString (14:14) = '-'
	timeString (17:17) = '-'
		
ELSE
	timeString = '                    '
END IF

string = TRIM(pathOut) // TRIM(timeString) // 'reservoirs.tab'

CALL TableExport (tab, string )


!create new table for diverted discharge
CALL TableNew ( tab )

!populate table
string = 'diverted discharge'
CALL TableSetId ( tab, string)

IF ( PRESENT (time) ) THEN
  timeString = time
  string = 'diverted discharge at: ' // timeString
ELSE
  string = 'diverted discharge at the end of simulation' 
END IF
CALL TableSetTitle ( tab, string)

!Allocate variables
CALL TableSetRowCol ( tab, nReservoirsWithDiversion, 3 )
IF ( ALLOCATED ( row ) ) THEN
    DEALLOCATE ( row )
END IF
ALLOCATE ( row (3) )

!set column header and unit
CALL TableSetColHeader (tab, 1, 'id')
CALL TableSetColHeader (tab, 2, 'Qin')
CALL TableSetColHeader (tab, 3, 'Qout')

CALL TableSetColUnit (tab, 1, '-')
CALL TableSetColUnit (tab, 2, 'm3/s')
CALL TableSetColUnit (tab, 3, 'm3/s')

!fill in rows
currentReservoir => pools

DO i = 1, nReservoirs
    IF ( currentReservoir % bypassIsPresent ) THEN
     !id
     row (1) = ToString (currentReservoir % id)
     !Qin
     row (2) = ToString (currentReservoir % bypass % QinChannel)
     !Qout
     row (3) = ToString (currentReservoir % bypass % QoutChannel)
     
     currentReservoir => currentReservoir % next
     
     CALL TableFillRow (tab, i, row)
    END IF
END DO

IF (PRESENT(time)) THEN
	timeString = time
	timeString = timeString (1:19) // '_'
	timeString (14:14) = '-'
	timeString (17:17) = '-'
		
ELSE
	timeString = '                    '
END IF

string = TRIM(pathOut) // TRIM(timeString) // 'reservoirs.tab'

CALL TableExport (tab, string, append = .TRUE. )

RETURN
END SUBROUTINE ReservoirSaveStatus